home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / t3_1 / doc.lha / documentation / manual / syntax.mss < prev    next >
Text File  |  1987-06-30  |  27KB  |  652 lines

  1. @part[SYNTAX, root "TMAN.MSS"]  @Comment{-*-System:TMAN-*-}
  2. @chap[Syntax]
  3. @label[SyntaxChapter]   @Comment{ref: implementation chapter}
  4. @label[Last T Chapter]  @Comment{ref: implementation chapter}
  5.  
  6.  
  7. The @Tau[] standard environment includes routines which perform
  8. syntactic and semantic analysis of @Tau[] programs.
  9. There are two such subsystems within @Tau[], corresponding to the
  10. language's two syntactic levels (see chapter @ref[semantics chapter]).
  11. These are the @i[reader] and the @i[compiler].
  12.  
  13. In an attempt to make each of these subsystems as generally useful and
  14. flexible as possible, they are not restricted to processing the language
  15. as described in this manual.  Instead, they each operate with respect to
  16. parameter clusters known as @iix[read tables], in the case of the
  17. reader, or @iix[syntax tables], in the case of the compiler.
  18.  
  19.  
  20. @section[The reader]
  21. @label[READER]          @Comment{ref: semantics}
  22.  
  23. The @iix[reader] is a procedure available in the standard environment as
  24. the value of the variable @tc[READ-OBJECT].  Conceptually, the reader
  25. coerces a stream of characters (@ix[external representation]) to a stream of
  26. objects (internal representations) via a mechanism
  27. known as @i[parsing].
  28.  
  29. @AnEquivE[Tfn="READ",Efn="READ"]
  30. @desc[@el[](READ-OBJECT @i[stream] @i[read-table]) @yl[] @i[object] @r[or] @i[end-of-file]]
  31. @tc[READ-OBJECT] employs the @tc[READ-CHAR] (page @pageref[READ-CHAR])
  32. and @tc[UNREAD-CHAR] (page @pageref[UNREAD-CHAR]) operations in
  33. order to parse an object according to the stream's read table.
  34.  
  35. If the stream is empty, the end-of-file token is returned.
  36.  
  37. @tc[READ-OBJECT] is called by the default method for the @tc[READ]
  38. operation (page @pageref[READ]), so the reader is usually invoked
  39. indirectly by calling
  40. @tc[READ], not by calling @tc[READ-OBJECT] directly.  When invoked
  41. from @tc[READ], the second argument to @tc[READ-OBJECT] is obtained
  42. by calling the @tc[STREAM-READ-TABLE] operation on the stream.
  43. @EndDesc[READ-OBJECT]
  44.  
  45. The reader works as follows:
  46.  
  47. Any whitespace characters (space, tab, newline, carriage return, line
  48. feed, or form feed) are read and ignored.  A non-whitespace character is
  49. obtained; call it @i[c].
  50. @index[Whitespace]
  51.  
  52. If @i[c] is a read-macro character, the reader invokes a specialist routine
  53. to handle a syntactic construct introduced by the read-macro character.
  54.  
  55. If @i[c] is not a read-macro character, then characters are read and
  56. saved until a @i[delimiter] character is read.  A delimiter character is
  57. either a whitespace character, or one of the following: @tc[(] (left
  58. parenthesis), @tc[)] (right parenthesis), @tc<[>, @tc<]>, @tc<{>,
  59. @tc<}>, or @tc[;] (semicolon).  If the sequence of characters beginning
  60. with @i[c] and going up to but not including the delimiter is parsable
  61. as a number, then the sequence is converted to a number, which is
  62. returned.
  63. Otherwise the sequence is converted to a symbol.
  64. @index[Numbers]
  65. @index[Symbols]
  66. @index[Delimiter characters]
  67. @index[Constituent characters]
  68.  
  69. The @i[escape character], backslash (@tc[\]), may be used within a
  70. run of constituent characters to include unusual characters in a
  71. symbol's print name.  In this case, the escaped character (i.e. the character
  72. following the escape character) is treated as if it were a constituent
  73. character, and is not converted to upper case if it is a lower case
  74. letter.  For example:
  75.   @begin[ProgramExample]
  76. abc\;def  @r[reads the same as]  #[Symbol "ABC;DEF"]
  77. \a\bcdef  @r[reads the same as]  #[Symbol "abCDEF"]
  78. \12345    @r[reads the same as]  #[Symbol "12345"]
  79. \'12345   @r[reads the same as]  #[Symbol "'12345"]
  80.   @end[ProgramExample]
  81.  
  82. @dc{ talk about dot? }
  83.  
  84. The following are standard read-macro characters:
  85.  
  86. @begin[description]
  87.  
  88. @tc["]@\Doublequote: introduces a string.  Characters are read until another doublequote
  89. character is found which does not immediately follow a backslash (@tc[\]),
  90. and a string is returned.  Within a string, backslash acts as an escape
  91. character, so that doublequotes and backslashes may appear in strings.
  92. @index[strings]
  93.  
  94. @tc[']@\Quote: @tc['@i[object]] reads the same as @tc[(QUOTE @i[object])].
  95. @tindex[QUOTE]
  96.  
  97. @tc[(]@\Left parenthesis: begins a list.@index[parentheses]
  98.  
  99. @tc[)]@\Right parenthesis: ends a list or vector, and is illegal in other
  100. contexts.
  101.  
  102. @tc[`]@\Backquote: see section @ref[backquote section].@index[Backquote]
  103.  
  104. @tc[,]@\Comma: this is part of the backquote syntax.
  105.  
  106. @tc[;]@\Semicolon: introduces a comment.  Characters are read and discarded
  107. until a newline is encountered, at which point the parsing process starts over.
  108. @label[SEMICOLON]
  109. @index[Comments]
  110.  
  111. @tc[#]@\Sharp-sign: another dispatch to a specialist routine is
  112. performed according to the character following the @tc[#].
  113. @end[description]
  114.  
  115. Standard sharp-sign forms:
  116.  
  117. @begin[description]
  118. @tc[#\]@\Character syntax.  See section @ref[character syntax].
  119.  
  120. @tc[#x]@\@ix[Hexadecimal] input.  An integer following the @tc[#x]
  121. is read in base 16.
  122.  
  123. @tc[#o]@\@ix[Octal] input.  An integer following the @tc[#o] is read in base 8.
  124.  
  125. @tc[#b]@\Binary input.  An integer following the @tc[#b] is read in base 2.
  126.  
  127. @tc[#(...)]@\Vector.  The elements of a vector are read between the parentheses,
  128. and the vector is returned.
  129. @index[Vectors]
  130.  
  131. @tc{#[...]}@\This syntax is used for certain kinds of re-readable objects.
  132. It also provides an alternate syntax for characters and symbols.
  133. The brackets enclose a sequence of objects; the first should be a symbol
  134. which keys the type of the resulting object, e.g. @tc[CHAR] or @tc[SYMBOL].
  135. @index[Characters]@index[Symbols]
  136. For example,
  137.   @begin[ProgramExample]
  138. #[Char 65]       @r[represents the same object as]  #\A
  139. #[Symbol "FOO"]  @r[represents the same object as]  FOO
  140.   @end[ProgramExample]
  141. This syntax is used by the printer when necessary, for example:
  142.   @begin[ProgramExample]
  143. (STRING->SYMBOL "")  @ev[]  #[Symbol ""]
  144. (ASCII->CHAR 128)    @ev[]  #[Char 128]
  145.   @end[ProgramExample]
  146.  
  147. @tc[#{...}]@\This is the syntax used by the printer for objects which
  148. have no reader syntax.  When the reader encounters the sequence @tc[#{]
  149. it signals an error.
  150. @end[description]
  151.  
  152.  
  153. @section[Read tables and read macros]
  154. @label[READTABLES]      @Comment{ref: semantics chapter, streams chapter}
  155.  
  156. @ix[Read tables] package a number of parameters for use by programs which
  157. parse, generate, or otherwise manipulate external syntax of programs and
  158. objects.  In particular, every read table contains a table which
  159. maps characters to objects which describe their lexical
  160. properties.
  161.  
  162. There is a standard read table which contains the standard read syntax
  163. for all characters.  In order to define nonstandard read syntax, one
  164. must create a new read table using @tc[MAKE-READ-TABLE], and arrange
  165. for @tc[READ-OBJECT] to use that read table instead of the standard
  166. read table, e.g. by doing @wt[(SET (STREAM-READ-TABLE ...) ...)].
  167.  
  168. @begin[group]
  169. @desc[(MAKE-READ-TABLE @i[read-table identification]) @yl[] @i[new-read-table]]
  170. Creates a new read table which is a copy of @i[read-table].
  171. @i[Identification] serves for debugging purposes only.
  172.   @begin[ProgramExample]
  173. (DEFINE *MY-READ-TABLE*
  174.   (MAKE-READ-TABLE *STANDARD-READ-TABLE* '*MY-READ-TABLE*))
  175.   @end[ProgramExample]
  176. @EndDesc[MAKE-READ-TABLE]
  177. @end[group]
  178.  
  179. @desc[*STANDARD-READ-TABLE* @yl[] @i[read-table]]
  180. The standard @Tau[] read table.
  181. @EndDesc[*STANDARD-READ-TABLE*]
  182.  
  183. @desc[*VANILLA-READ-TABLE* @yl[] @i[read-table]]
  184. The value of @tc[*VANILLA-READ-TABLE*] is a read table in which all
  185. all graphic characters have ordinary non-read-macro constituent
  186. syntax, whitespace characters have whitespace syntax, and
  187. other characters (e.g. control characters) are illegal.
  188.   @begin[ProgramExample]
  189. (WITH-INPUT-FROM-STRING (STREAM " foo () ")
  190.   (SET (STREAM-READ-TABLE STREAM) *VANILLA-READ-TABLE*)
  191.   (LIST (READ STREAM) (READ STREAM)))
  192. @ev[]  (FOO #[Symbol "()"])
  193.   @end[ProgramExample]
  194. @EndDesc[*VANILLA-READ-TABLE*]
  195.  
  196. @info[NOTES="Settable"]
  197. @desc[(READ-TABLE-ENTRY @i[table character]) @yl[] @i[syntax]]
  198. Access @i[character]'s read syntax in @i[table].
  199. The entry for a given character is some object which represents the
  200. character's lexical properties, for example, whether it is
  201. a constituent, whitespace, or read-macro character.
  202. For read-macro characters, the entry is a procedure
  203. for parsing the read-macro construct.
  204. @index[Read macros]
  205.  
  206. Values suitable to be stored in read tables may be obtained
  207. by accessing existing entries in the standard read table.  For example:
  208.   @begin[ProgramExample]
  209. (SET (READ-TABLE-ENTRY *MY-READ-TABLE* #\;)
  210.      (READ-TABLE-ENTRY *STANDARD-READ-TABLE* #\:))
  211.   @end[ProgramExample]
  212. makes the read syntax of semicolon in @tc[*MY-READ-TABLE*] be the
  213. same as the standard read syntax of colon (which is a
  214. contituent character).
  215.  
  216. To define a read macro, do 
  217.   @begin[ProgramExample]
  218. (SET (READ-TABLE-ENTRY @i[read-table] @i[character]) @i[procedure])
  219.   @end[ProgramExample]
  220. where @i[procedure] is a procedure taking two arguments: a stream
  221. and a character.  The stream is the stream which is currently being
  222. parsed by @tc[READ-OBJECT].  It may be passed as the stream argument
  223. to input routines like @tc[READC] and @tc[READ-REFUSING-EOF] if the
  224. read-macro needs to parse further characters from the input stream.
  225. The character is the character which caused the read macro to be
  226. invoked; that is, it is the character under which the procedure is
  227. stored in the read table.
  228.  
  229. Example:
  230. @begin[ProgramExample]
  231. (SET (READ-TABLE-ENTRY *MY-READ-TABLE* #\')
  232.      (LAMBDA (STREAM CH)
  233.        (IGNORE CH)
  234.        (LIST 'QUOTE (READ-REFUSING-EOF STREAM))))
  235. @end[ProgramExample]
  236. Note that the standard read table and the vanilla read table
  237. are immutable, and so their entries may not be changed.
  238. @EndDesc[READ-TABLE-ENTRY]
  239.  
  240. @desc[*NOTHING-READ* @yl[] @i[object]]
  241. Read macros should return this object, which is treated specially
  242. by the reader, if they want to return no object.
  243. For example, the semi-colon (comment) read-macro might be defined as follows:
  244.   @begin[ProgramExample]
  245. (SET (READ-TABLE-ENTRY *MY-READ-TABLE* #\;)
  246.      (LAMBDA (STREAM CH)
  247.         (ITERATE LOOP ()
  248.           (LET ((C (READC STREAM)))
  249.             (COND ((EOF? C) C)
  250.                   ((CHAR= C #\NEWLINE) *NOTHING-READ*)
  251.                   (ELSE (LOOP)))))))
  252.   @end[ProgramExample]
  253. @EndDesc[*NOTHING-READ*]
  254.  
  255. @info[NOTES="Operation"]
  256. @desc[(DELIMITING-READ-MACRO? @i[procedure]) @yl[] @i[boolean]]
  257. If an object which returns true to the @tc[DELIMITING-READ-MACRO?] operation is
  258. stored in a read table under a given character, then the reader will
  259. treat the character as a delimiter (non-constituent) character.
  260. By default, read-macro procedures return false to this predicate.  Thus
  261. to make a read-macro character be a delimiting character also (as
  262. are parentheses and semicolon in the standard read table), its
  263. read table entry should handle this operation by returning true.
  264.   @begin[ProgramExample]
  265. (SET (READ-TABLE-ENTRY *MY-READ-TABLE* #\~)
  266.      (OBJECT (LAMBDA (STREAM CH)
  267.                ...)
  268.              ((DELIMITING-READ-MACRO? SELF) T)))
  269.   @end[ProgramExample]
  270. @EndDesc[DELIMITING-READ-MACRO?]
  271.  
  272. @desc[(MAKE-LIST-READER) @yl[] @i[list-reader]]
  273. The two procedures @tc[MAKE-LIST-READER] and @tc[LIST-TERMINATOR]
  274. can be used together to define read macros which behave syntactically
  275. like parentheses.
  276.  
  277. Each call to @tc[MAKE-LIST-READER] returns an object which is a
  278. procedure of two arguments called a @i[list reader.]  Calling
  279. @tc[LIST-TERMINATOR] on a list reader will return another object called
  280. its @i[list terminator.]
  281.  
  282. List readers and terminators are suitable for entry in read tables.
  283. A list reader acts as a read macro which reads a sequence of objects,
  284. terminated by a character whose read syntax is the corresponding list
  285. terminator.  For example, the standard syntax for left and right
  286. parentheses might be defined as follows:
  287.   @begin[ProgramExample]
  288. (LET ((LIST-READER (MAKE-LIST-READER)))
  289.   (SET (READ-TABLE-ENTRY *STANDARD-READ-TABLE* #\LEFT-PAREN)
  290.        LIST-READER)
  291.   (SET (READ-TABLE-ENTRY *STANDARD-READ-TABLE* #\RIGHT-PAREN)
  292.        (LIST-TERMINATOR LIST-READER)))
  293.   @end[ProgramExample]
  294.  
  295. Like any read-macro procedure, a list reader is a procedure of two
  296. arguments.  The first argument must be a stream, and the second is
  297. ignored.  Thus instead of being stored in a read table, it may be
  298. called from another read-macro procedure.  For example, the following
  299. makes @tc<[...]> an alternative read syntax for vectors:
  300.   @begin[ProgramExample]
  301. (LET ((LIST-READER (MAKE-LIST-READER)))
  302.   (SET (READ-TABLE-ENTRY *MY-READ-TABLE* #\LEFT-BRACKET)
  303.        (OBJECT (LAMBDA (STREAM CH)
  304.                  (LIST->VECTOR (LIST-READER STREAM CH)))
  305.                ((DELIMITING-READ-MACRO? SELF) T)))
  306.   (SET (READ-TABLE-ENTRY *MY-READ-TABLE* #\RIGHT-BRACKET)
  307.        (LIST-TERMINATOR LIST-READER)))
  308.   @end[ProgramExample]
  309.  
  310. List readers and terminators handle the @tc[DELIMITING-READ-MACRO?]
  311. operation by returning true.
  312. @EndDesc[MAKE-LIST-READER]
  313.  
  314. @desc[(LIST-TERMINATOR @i[list-reader]) @yl[] @i[list-terminator]]
  315. Given a list reader, returns its list terminator.  See @tc[LIST-READER],
  316. above.
  317. @EndDesc[LIST-TERMINATOR]
  318.  
  319.  
  320. @section[Standard compiler]
  321.  
  322. A @iixs[compiler] is a procedure which accepts an expression and a
  323. syntax table, and returns a @i[compiled code] object.  A compiled
  324. code object may be executed in a given environment.  Note that
  325. the term @qu"compiler" is used in a technical sense
  326. and encompasses not only compilers such as TC (section @ref[COMFILE]) which
  327. produce machine instructions, but also programs such as the standard
  328. compiler (which is called by @tc[EVAL]) which operate internally by
  329. producing intermediate code or by interpreting source code directly.
  330. Often programs like these are called @i[interpreters] instead of
  331. @i[compilers.]
  332.  
  333. @index[Expression syntax]
  334.  
  335. A given @Tau[] implementation may have several compilers.
  336. @tc[STANDARD-COMPILER] should be one of these compilers.
  337. @Timp[] 2.7 also provides a compiler called TC, which is
  338. described in section @ref[COMFILE].
  339.  
  340. @desc[(EVAL @i[expression] @i[environment]) @yl[] @i[object]]
  341. Evaluates @i[expression] in @i[environment].  Evaluation is performed as
  342. a two-stage process: first, the standard compiler compiles the
  343. expression, producing a compiled code object; then the compiled code
  344. object is invoked in the given environment.
  345.   @begin[TEG]
  346. (EVAL @i[expression] @i[environment])
  347.   @ce[]
  348. (RUN-COMPILED-CODE (STANDARD-COMPILER @i[expression]
  349.                                       (ENV-SYNTAX-TABLE @i[environment]))
  350.                    @i[environment])
  351.   @end[TEG]
  352. @EndDesc[EVAL]
  353.  
  354. @desc[(STANDARD-COMPILER @i[expression] @i[syntax-table]) @yl[] @i[compiled-code]]
  355. Compiles @i[expression].  An implementation of @Tau[] may provide several
  356. compilers, of which @tc[STANDARD-COMPILER] will be the one which is
  357. invoked by @tc[EVAL].
  358. @EndDesc[STANDARD-COMPILER]
  359.  
  360. @desc[(RUN-COMPILED-CODE @i[compiled-code] @i[environment]) @yl[] @i[object]]
  361. Invokes a compiled code object.
  362.     @BeginInset[Bug:]
  363.     In @Timp[] 2.7, the environment passed to @tc[RUN-COMPILED-CODE]
  364.     must be the same as the one whose syntax table was passed
  365.     to @tc[STANDARD-COMPILER].
  366.     @EndInset[]
  367. @EndDesc[RUN-COMPILED-CODE]
  368.  
  369.  
  370. @section[Syntax tables]
  371.  
  372. @label[Syntax tables section]   @Comment{ref: semantics}
  373.  
  374. @index[Syntax tables]
  375. @index[Reserved words]
  376. @index[Special forms]
  377. A syntax table maps symbols to @iix[syntax descriptors].  Every syntax
  378. descriptor is itself either a macro expander, or a unique token
  379. identifying a primitive special form type.
  380.  
  381. Every locale has an associated syntax table.  A locale's syntax table
  382. contains definitions of special forms which are local to the locale.  Each
  383. such syntax table inherits entries lexically from the syntax tables
  384. of enclosing locales.
  385.  
  386. @iix[Macros] provide a mechanism for extending the syntax of @Tau[]
  387. by means of source-to-source transformations.
  388. As in many Lisp dialects, the macro facility in @Tau[] provides a powerful
  389. tool for amplifying the expressiveness of the language.  But like any
  390. powerful tool, macros may be abused.  They may easily lead to programs
  391. that are very hard to understand.
  392.  
  393. Macros are defined by entering syntax descriptor objects known as
  394. @iix[macro expanders] into syntax tables; see
  395. @tc[SYNTAX-TABLE-ENTRY] and @tc[DEFINE-SYNTAX], below.
  396. Macros may also be defined locally to a file or expression using
  397. @tc[DEFINE-LOCAL-SYNTAX] or @tc[LET-SYNTAX].
  398.  
  399. Procedure integration is preferable to the use of macros in situations
  400. where either would be applicable.  See @tc[DEFINE-INTEGRABLE], page
  401. @pageref[DEFINE-INTEGRABLE].
  402.  
  403.  
  404. @desc[(ENV-SYNTAX-TABLE @i[environment]) @yl[] @i[syntax-table]]
  405. Returns the syntax table associated with @i[environment].
  406. @EndDesc[ENV-SYNTAX-TABLE]
  407.  
  408. @desc[(MAKE-SYNTAX-TABLE @i[syntax-table] @i[identification]) @yl[] @i[syntax-table]]
  409. Creates a new syntax table inferior to the given syntax table.
  410. Note that syntax tables are created implicitly by @tc[MAKE-LOCALE]
  411. (page @pageref[MAKE-LOCALE]).
  412. @EndDesc[MAKE-SYNTAX-TABLE]
  413.  
  414. @desc[*STANDARD-SYNTAX-TABLE* @yl[] @i[syntax-table]]
  415. A syntax table with entries for all standard @Tau[] reserved words.
  416.   @begin[ProgramExample]
  417. *STANDARD-SYNTAX-TABLE*  @ce[]  (ENV-SYNTAX-TABLE-ENTRY *STANDARD-ENV*)
  418.   @end[ProgramExample]
  419. @EndDesc[*STANDARD-SYNTAX-TABLE*]
  420.  
  421. @info[NOTES="Settable"]
  422. @desc[(SYNTAX-TABLE-ENTRY @i[syntax-table] @i[symbol]) @yl[] @i[descriptor] @r[or] @i[false]]
  423. Accesses the syntax descriptor associated with @i[symbol] in
  424. @i[syntax-table].  Returns false if there is no such entry.
  425.   @begin[ProgramExample]
  426. (SYNTAX-TABLE-ENTRY *STANDARD-SYNTAX-TABLE* 'QUOTE)  @ev[]  #{Syntax QUOTE}
  427. (SYNTAX-TABLE-ENTRY *STANDARD-SYNTAX-TABLE* 'CAR)    @ev[]  @r[false]
  428.   @end[ProgramExample]
  429. Syntax table entries may be created or altered using
  430. @wt[(SET (SYNTAX-TABLE-ENTRY ...) ...)]
  431. or by using @tc[DEFINE-SYNTAX].  On assignment, @i[descriptor] may
  432. be false, in which case @i[symbol] loses any syntax table entry it
  433. may have had.  This allows it to be bound as a variable using
  434. @tc[DEFINE] or @tc[LET], for example.
  435. @enddesc[SYNTAX-TABLE-ENTRY]
  436.  
  437.  
  438. @section[Defining syntax]
  439.  
  440. @descN[
  441. F1="(DEFINE-SYNTAX @i[symbol] @i[descriptor]) @yl[] @i[undefined]",
  442. FN1="DEFINE-SYNTAX",
  443. F2="(DEFINE-SYNTAX (@i[symbol] . @i[vars]) . @i[body]) @yl[] @i[undefined]"
  444. ]
  445. Sets @i[symbol]'s syntax table entry in the syntax table of the
  446. environment in which the @tc[DEFINE-SYNTAX] form is being evaluated.
  447. The second form is an abbreviation for an equivalent expression
  448. of the first form involving @tc[MACRO-EXPANDER]:
  449.   @begin[ProgramExample]
  450. (DEFINE-SYNTAX (@i[symbol] . @i[variables]) . @i[body])
  451.   @ce[]
  452. (DEFINE-SYNTAX @i[symbol]
  453.   (MACRO-EXPANDER (@i[symbol] . @i[variables]) . @i[body]))
  454.   @end[ProgramExample]
  455. Macros and @tc[MACRO-EXPANDER] are explained below.
  456.  
  457. As with @tc[(SET (SYNTAX-TABLE-ENTRY ...) ...)], @i[descriptor] may
  458. be false, in which case @i[symbol] loses any syntax table entry it
  459. may have had.  This allows it to be bound as a variable using
  460. @tc[DEFINE] or @tc[LET], for example.
  461.  
  462. Note that @tc[DEFINE-SYNTAX] forms have no effect
  463. at compile time.  Using them indiscriminately may lead to code
  464. which behaves differently depending on what compiler is being used.
  465. For example, a use of the special form defined by a @tc[DEFINE-SYNTAX]
  466. form later on in the same file in which the @tc[DEFINE-SYNTAX] form
  467. occurs may be seen as a valid special form reference by the standard
  468. compiler, but may be treated as a call by TC.
  469.  
  470.   @begin[ProgramExample]
  471. (DEFINE-SYNTAX (REPEAT N . CODE)
  472.   `(LET ((COUNT ,N)
  473.          (THUNK (LAMBDA () ,@@CODE)))
  474.      (DO ((COUNT COUNT (- COUNT 1)))
  475.          ((<= COUNT 0) NIL)
  476.        (THUNK))))
  477.   @end[ProgramExample]
  478. @enddescN[]
  479.  
  480.  
  481. @section[Local syntax]
  482.  
  483. Reserved words may be defined at compile time using @tc[LET-SYNTAX]
  484. and @tc[DEFINE-LOCAL-SYNTAX].  Syntax defined this way is called
  485. @iix[local syntax] and is in effect only at compile time, not at run
  486. time.
  487.  
  488. Local syntax is block structured, much as variables are.  The outermost
  489. local syntax contour is the point at which a compiler is invoked,
  490. which usually means a file boundary.  Inner contours are introduced
  491. by @tc[LET-SYNTAX] forms.
  492.  
  493. Put another way, a local syntax table is created whenever a compiler
  494. is invoked (@tc[LOAD], @tc[COMFILE], @tc[EVAL]) and whenever a
  495. @tc[LET-SYNTAX] form is compiled.  Entries are created in a local
  496. syntax table at compile time for syntax defined initially by the
  497. @tc[LET-SYNTAX] form and later when the compiler encounters
  498. @tc[DEFINE-LOCAL-SYNTAX] forms.  The syntax table is used at compile
  499. time and is otherwise unavailable.
  500.  
  501. @desc[(LET-SYNTAX @i[specs] . @i[body]) @yl[] @i[value-of-body]]
  502. Defines macros locally to @i[body].  Yields the value of @i[body],
  503. an implicit block.  Each @i[spec] should be either
  504.     @begin[ProgramExample]
  505. (@i[symbol] @i[descriptor])
  506.     @end[ProgramExample]
  507. or
  508.     @begin[ProgramExample]
  509. ((@i[symbol] . @i[vars]) . @i[body])
  510.     @end[ProgramExample]
  511. in analogy to @tc[DEFINE-SYNTAX].
  512.  
  513. The @i[descriptor] and @i[body] forms in @i[specs] will not necessarily
  514. run in an environment which is at all related to the environment in
  515. which the program in which the @tc[LET-SYNTAX] form occurred will
  516. be run, because compilation may occur independently of execution.
  517. TC executes these forms in @tc[(TC-MACRO-DEFINITION-ENV)]; see page
  518. @pageref[TC-MACRO-DEFINITION-ENV].  The standard compiler uses the
  519. locale with which the syntax table passed to it is associated.  This
  520. is implementation-dependent, and subject to change.  For this reason,
  521. it is best to write local macros in such a way that no free variables
  522. or special forms are used, other than those in the standard system
  523. environment, that is, those defined to be part of the @Tau[] language.
  524.  
  525. This disclaimer does not apply to the @i[body] of the @tc[LET-SYNTAX] form,
  526. which is evaluated (except for syntax) exactly as if the @tc[LET-SYNTAX]
  527. expression were a @tc[BLOCK] expression.
  528.     @begin[ProgramExample]
  529. (LET-SYNTAX ((KWOTE (SYNTAX-TABLE-ENTRY *STANDARD-SYNTAX-TABLE*
  530.                                         'QUOTE)))
  531.   (KWOTE (A B C)))@tindex[KWOTE]
  532. @ev[]  (A B C)
  533.  
  534. (LET-SYNTAX ((SET NIL)) (LET ((SET LIST) (X 5)) (SET X 8)))  @ev[]  (5 8)
  535.  
  536. (LET-SYNTAX (((MAC X) `'(X = ,X))) (MAC Y))  @ev[]  (X = Y)
  537.     @end[ProgramExample]
  538.  
  539.     @BeginInset[Bug:]
  540.     @Timp[] 2.7 doesn't implement @tc[LET-SYNTAX].
  541.     @EndInset[]
  542. @EndDesc[LET-SYNTAX]
  543.  
  544. @info[NOTES="Special form"]
  545. @descN[
  546. F1="(DEFINE-LOCAL-SYNTAX @i[symbol] @i[descriptor]) @yl[] @i[undefined]",
  547. FN1="DEFINE-LOCAL-SYNTAX",
  548. F2="(DEFINE-LOCAL-SYNTAX (@i[symbol] . @i[vars]) . @i[body]) @yl[] @i[undefined]",
  549. ]
  550. Defines syntax locally to the body of the nearest enclosing
  551. @tc[LET-SYNTAX] form, or, if the @tc[DEFINE-LOCAL-SYNTAX] does not
  552. appear inside a @tc[LET-SYNTAX] form, then to the file or outermost
  553. expression in which it occurs.  Forward references are not defined
  554. to work; the @tc[DEFINE-LOCAL-SYNTAX] form should appear prior to any use of
  555. @i[symbol] as a reserved word.
  556.  
  557. The syntax of @tc[DEFINE-LOCAL-SYNTAX] is analogous to that of
  558. @tc[DEFINE-SYNTAX].
  559.  
  560. In general, @tc[DEFINE-LOCAL-SYNTAX] should be used for syntax which is
  561. to be available only within the file in which it occurs.  If
  562. a syntax definition is needed for several files, then they
  563. should be made available in some locale's syntax table by evaluating
  564. @tc[DEFINE-SYNTAX] forms in that locale, and then that locale's syntax table
  565. should be used when compiling or loading the file (see the @tc[SYNTAX-TABLE]
  566. file header clause, page @pageref[SYNTAX-TABLE]).
  567.  
  568.     @begin[group]
  569.     @BeginInset[Note:]
  570.     To ease incremental debugging, the standard compiler in @Timp[]
  571.     2.7 causes syntax defined with @tc[DEFINE-LOCAL-SYNTAX] to be
  572.     retained indefinitely; that is, they are entered into the syntax
  573.     table of the locale which was passed to @tc[LOAD].  Programs should
  574.     not rely on this feature,
  575.     however, or code may behave differently when compiled using TC.
  576.     @EndInset[]
  577.     @end[group]
  578. @EndDescN[]
  579.  
  580.  
  581. @section[Macro expanders]
  582.  
  583. @info[NOTES="Special form"]
  584. @desc[(MACRO-EXPANDER (@i[identification] . @i[variables]) . @i[body]) @yl[] @i[macro-expander]]
  585. Yields a macro expander.  A macro expander is a kind of syntax
  586. descriptor, and may therefore be stored in a syntax table.  When a
  587. compiler using a symbol table @i[S] encounters a form whose car is
  588. a symbol, and the entry in @i[S] for that symbol is the object yielded
  589. by a @tc[MACRO-EXPANDER]-expression, then the macro expander
  590. is invoked; that is, its
  591. @i[variables] are bound to the rest of form (as with one level of
  592. @tc[DESTRUCTURE] binding), the @i[body] (an implicit block) is evaluated,
  593. and the value is returned to the compiler.  The compiler then compiles that
  594. form in place of the original one.
  595.  
  596. The lexical context of @i[body] is that of the @tc[MACRO-EXPANDER] form
  597. (augmented by the bindings of @i[variables], of course), as with
  598. @tc[LAMBDA].
  599.   @begin[ProgramExample]
  600. (DEFINE M (MACRO-EXPANDER (FOO X Y Z) `(LIST 'FIRST ',X ,Y ,Z)))
  601. (INVOKE-MACRO-EXPANDER M '(BAR QUOTED (+ 1 2) (* 3 4)))
  602.   @ev[]  (LIST 'FIRST 'QUOTED  (+ 1 2) (* 3 4))
  603.  
  604. (DEFINE L (MAKE-LOCALE *STANDARD-ENV* NIL))
  605. (SET (SYNTAX-TABLE-ENTRY (ENV-SYNTAX-TABLE L) 'BAR) M)
  606.  
  607. (EVAL '(BAR QUOTED (+ 1 2) (* 3 4)) L)  @ev[]  (FIRST QUOTED 3 12)
  608.  
  609. (DEFINE-SYNTAX FOO
  610.   (MACRO-EXPANDER (FOO THING FORM)
  611.     `(LIST ,FORM ',THING)))
  612.  
  613. (FOO (CONS 1 2) (CONS 3 5))  @ev[]  ((3 . 5) (CONS 1 2))
  614.   @end[ProgramExample]
  615.  
  616. @tc[DESTRUCTURE] (page @PageRef[destructure]) and
  617. backquote (page @PageRef[backquote section]) are useful in writing
  618. macro expansion procedures, the first for taking apart the
  619. form which is to be expanded, the second for constructing the resultant code
  620. from templates.
  621.  
  622. Note that for a macro definition to take effect at compile time, it
  623. must either be present in the syntax table being used by the
  624. compiler (see page @pageref[SYNTAX-TABLE]), or defined locally
  625. using @tc[LET-SYNTAX] or @tc[DEFINE-LOCAL-SYNTAX].
  626. @enddesc[MACRO-EXPANDER]
  627.  
  628. @desc[(MACRO-EXPANDER? @i[descriptor]) @yl[] @i[boolean]]
  629. Returns true if @i[descriptor], which must be a syntax descriptor,
  630. is a macro expander.
  631.     @begin[ProgramExample]
  632. (MACRO-EXPANDER? (MACRO-EXPANDER (FOO X) X))  @ev[]  @r[true]
  633.     @end[ProgramExample]
  634. @enddesc[MACRO-EXPANDER?]
  635.  
  636. @desc[(INVOKE-MACRO-EXPANDER @i[descriptor] @i[form]) @yl[] @i[new-form]]
  637. Invokes the macro expansion procedure for @i[descriptor], which must
  638. be a macro expander.  (See @tc[MACRO-EXPANDER], above.)
  639.     @begin[ProgramExample]
  640. (INVOKE-MACRO-EXPANDER (MACRO-EXPANDER (FOO X) `(LAMBDA () ,X))
  641.                        '(BAZ (+ 1 2)))
  642.   @ev[]
  643. (LAMBDA () (+ 1 2))
  644.     @end[ProgramExample]
  645. @enddesc[INVOKE-MACRO-EXPANDER]
  646.  
  647. @desc[(MACRO-EXPAND @i[form syntax-table]) @yl[] @i[new-form]]
  648. Performs one macro expansion on the @i[form], if it is a list whose
  649. car is a symbol, there is an entry in the given @i[syntax-table] for
  650. that symbol, and that entry is a macro expander.
  651. @EndDesc[MACRO-EXPAND]
  652.